PlantsAllometrics.f90 Source File

Define relations between key characteristic dimensions of trees and other properties



Source Code

!! Define  relations between key characteristic 
!! dimensions of trees and other properties
!|author:  <a href="mailto:giovanni.ravazzani@polimi.it">Giovanni Ravazzani</a>
! license: <a href="http://www.gnu.org/licenses/">GPL</a>
!    
!### History
!
! current version  1.0 - 29st April 2019  
!
! | version  |  date       |  comment |
! |----------|-------------|----------|
! | 1.0      | 29/Apr/2019 | Original code |
!
!### License  
! license: GNU GPL <http://www.gnu.org/licenses/>
!
!### Module Description 
! Module defining quantitative relations between some key 
! characteristic dimensions of trees (usually fairly easy 
! to measure) and other properties (often more difficult to assess).
! 
MODULE PlantsAllometrics

! Modules used:


USE DataTypeSizes, ONLY : &
   ! Imported Type Definitions:
   short, float

USE Units, ONLY : &
    ! imported parameters:
    Pi, hectare

IMPLICIT NONE

!global routines:
PUBLIC :: DBHvsStemBiomass
PUBLIC :: StemBiomassVsDBH
PUBLIC :: HeightVsDBH
PUBLIC :: CrownDiameter
PUBLIC :: CanopyCover

!local routines:
PRIVATE :: DBHDCeff


!=======
    CONTAINS
!=======
    
!==============================================================================
!| Description:
!  relationship between DBH (Diameter at Brest Height) and stem biomass.
!
!  Reference: 
!
!    Peter Sands, Adaptation of 3-PG to novel species :
!     guidelines for data collection and parameter assignment, 
!    Technical Report 141, EQ. 8
!   http://3pg.sites.olt.ubc.ca/files/2014/04/3-PG-guidelines.TR141.pdf
FUNCTION  DBHvsStemBiomass &
!
(ws, n, as, ns) &
!
RESULT (dbh)


IMPLICIT NONE

! Arguments with intent(in):
REAL (KIND = float), INTENT(IN) :: ws !!stem biomass (t)
REAL (KIND = float), INTENT(IN) :: n !!number of trees
REAL (KIND = float), INTENT(IN) :: as !!scaling coefficient
REAL (KIND = float), INTENT(IN) :: ns !!scaling exponent

!local declarations:
REAL (KIND = float) :: dbh !!diameter at brest height (cm)

!------------end of declaration------------------------------------------------ 

dbh = ( ws / (n * as) ) ** (1. / ns)

RETURN
END FUNCTION DBHvsStemBiomass


!==============================================================================
!| Description:
!  relationship between stem biomass andDBH (Diameter at Brest Height).
!
!  Reference: 
!
!    Peter Sands, Adaptation of 3-PG to novel species :
!     guidelines for data collection and parameter assignment, 
!    Technical Report 141, EQ. 8
!   http://3pg.sites.olt.ubc.ca/files/2014/04/3-PG-guidelines.TR141.pdf
FUNCTION  StemBiomassVsDBH &
!
(dbh, n, as, ns) &
!
RESULT (ws)


IMPLICIT NONE

! Arguments with intent(in):
REAL (KIND = float), INTENT(IN) :: dbh !!  diameter at brest height (cm) 
REAL (KIND = float), INTENT(IN) :: n !!  number of trees
REAL (KIND = float), INTENT(IN) :: as !!  scaling coefficient
REAL (KIND = float), INTENT(IN) :: ns !!  scaling exponent

!local declarations:
REAL (KIND = float) :: ws !!  stem biomass (t)

!------------end of declaration------------------------------------------------ 

! dbh = ( ws / (n * as) ) ** (1. / ns)  

RETURN
END FUNCTION StemBiomassVsDBH


!==============================================================================
!| Description:
!  relationship between tree height and DBH (Diameter at Brest Height).
!  Implements Chapman-Richards relationship
!
!  Reference: 
!
!    Wang, C. Biomass allometric equations for 10 co-occurring
!    tree species in Chinese temperate forests.
!    Forest Ecology and Management, 222, 9–16, 2006
FUNCTION  HeightVsDBH &
!
(dbh, cra, crb, crc) &
!
RESULT (height)


IMPLICIT NONE

! Arguments with intent(in):
REAL (KIND = float), INTENT(IN) :: dbh !!diameter at brest height (cm)
REAL (KIND = float), INTENT(IN) :: cra !!Chapman-Richards asymptotic maximum height
REAL (KIND = float), INTENT(IN) :: crb !!Chapman-Richards exponential decay parameter
REAL (KIND = float), INTENT(IN) :: crc !!Chapman-Richards shape parameter

!local declarations:
REAL (KIND = float) :: height !! tree eight (m)

!------------end of declaration------------------------------------------------ 

height = 1.3 + cra * ( 1. - EXP ( - dbh * crb) ) ** crc

RETURN
END FUNCTION HeightVsDBH

!==============================================================================
!| Description:
!  compute crown doameter (m)
!
! References:
!
!  Collalti, Alessio & Perugini, Lucia & Santini, Monia & Chiti, 
!  Tommaso & Nolè, Angelo & Matteucci, Giorgio & Valentini, Riccardo, 2014.
!  A process-based model to simulate growth in forests with complex structure: 
!  Evaluation and use of 3D-CMCC Forest Ecosystem Model in a deciduous forest 
!  in Central Italy, Ecological Modelling,  272(C), 362-378.
FUNCTION  CrownDiameter &
!
(dbh, den, denmin, denmax, dbhdcmin, dbhdcmax) &
!
RESULT (cd)


IMPLICIT NONE

!arguments with intent(in):
REAL (KIND = float), INTENT(IN) :: dbh !! diameter at brest height (cm)
REAL (KIND = float), INTENT(IN) :: den !! current tree density (trees/ha)
REAL (KIND = float), INTENT(IN) :: denmin !! minimum tree density (trees/ha)
REAL (KIND = float), INTENT(IN) :: denmax !! minimum tree density (trees/ha)
REAL (KIND = float), INTENT(IN) :: dbhdcmin !! minimum ratio between stem and crown diameters (m/cm)
REAL (KIND = float), INTENT(IN) :: dbhdcmax !! maximum ratio between stem and crown diameters (m/cm)

!local declarations:
REAL (KIND = float) :: cd !! returned result
REAL (KIND = float) :: dbhdc !! actual ratio between dbh and crown diameters (m/cm)

!-----------------------------------end of declarations------------------------

!compute actual dbhdc
dbhdc = DBHDCeff (dbhdcmin, dbhdcmax, den, denmin, denmax)

cd = dbh * dbhdc

RETURN
END FUNCTION CrownDiameter


!==============================================================================
!| Description:
!  compute canopy cover (0-1)
!
! References:
!
!  Collalti, Alessio & Perugini, Lucia & Santini, Monia & Chiti, 
!  Tommaso & Nolè, Angelo & Matteucci, Giorgio & Valentini, Riccardo, 2014.
!  A process-based model to simulate growth in forests with complex structure: 
!  Evaluation and use of 3D-CMCC Forest Ecosystem Model in a deciduous forest 
!  in Central Italy, Ecological Modelling,  272(C), 362-378.
FUNCTION  CanopyCover &
!
(dc, den) &
!
RESULT (cc)

IMPLICIT NONE

!arguments with intent(in):
REAL (KIND = float), INTENT(IN) :: dc !! crown diameter (m)
REAL (KIND = float), INTENT(IN) :: den !! tree density (trees/ha)

!local declarations:
REAL (KIND = float) :: cc !! returned result
REAL (KIND = float) :: dbhdc !! actual ratio between dbh and crown diameters (m/cm)

!-----------------------------------end of declarations------------------------


cc = Pi * dc ** 2. / 4. * den / hectare

!check boundary
IF ( cc > 1. ) THEN
    cc = 1.
END IF

IF ( cc < 0.) THEN
    cc = 0.
END IF


RETURN
END FUNCTION CanopyCover


!==============================================================================
!| Description:
!  Compute the actual ratio DBH-crown diameter: crown/dbh (m/cm)
FUNCTION  DBHDCeff &
!
(dbhdcmin, dbhdcmax, den, denmin, denmax) &
!
RESULT (dbhdc)

IMPLICIT NONE

!arguments with intent(in):
REAL (KIND = float), INTENT(IN) :: dbhdcmin !! minimum ratio between stem and crown diameters (m/cm)
REAL (KIND = float), INTENT(IN) :: dbhdcmax !! maximum ratio between stem and crown diameters (m/cm)
REAL (KIND = float), INTENT(IN) :: den !! current tree density (trees/ha)
REAL (KIND = float), INTENT(IN) :: denmin !! minimum tree density (trees/ha)
REAL (KIND = float), INTENT(IN) :: denmax !! minimum tree density (trees/ha)

!local declarations:
REAL (KIND = float) :: dbhdc !! returned result


!-----------------------------------end of declarations------------------------

dbhdc = ( dbhdcmax - dbhdcmin ) / ( denmax - denmin ) * &
           ( den - denmin ) + dbhdcmin

RETURN
END FUNCTION DBHDCeff

END MODULE PlantsAllometrics